TableReadUnit Subroutine

private subroutine TableReadUnit(lines, tab)

read unit of the columns of the table. Arguments: lines collection of strings that contain table information tab table to update

Arguments

Type IntentOptional Attributes Name
character(len=LINELENGTH), intent(in), POINTER :: lines(:)
type(Table), intent(out) :: tab

Variables

Type Visibility Attributes Name Initial
character(len=LINELENGTH), public :: before
integer(kind=long), public :: i
integer(kind=long), public :: par1
integer(kind=long), public :: par2
character(len=LINELENGTH), public :: string

Source Code

SUBROUTINE TableReadUnit &
  ( lines, tab )
  
! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringSplit, StringToUpper

IMPLICIT NONE

! Function arguments
! Scalar arguments with intent(in):
CHARACTER (LEN = LINELENGTH), INTENT (IN), POINTER :: lines (:)

! Array arguments with intent (out):
TYPE (Table), INTENT (OUT) :: tab
! Local scalars:
CHARACTER (LEN = LINELENGTH)  :: string
CHARACTER (LEN = LINELENGTH)  :: before
INTEGER (KIND = long) :: i
INTEGER (KIND = long) :: par1, par2

! Local Arrays:

!------------end of declaration------------------------------------------------

string = ''

! scan table to find line denoted by units keyword.
DO i = 1, SIZE (lines)
  string =  lines (i)
  CALL StringSplit ( ':', string, before)
  IF (  StringToUpper ( before(1:5)) == "UNITS" ) THEN !found units
    CALL StringSplit ( '#', string, before) !remove inline comments
    string = before
    EXIT
  END IF
END DO

!search for headers
DO i = 1, tab % noCols
  par1 = INDEX ( string, '[' )
  par2 = INDEX ( string, ']' )
  tab % col (i) % unit = string ( par1+1 : par2-1 )
  !erase part of the string already processed
  string = string ( par2+1 : LEN_TRIM (string) )   
END DO

END SUBROUTINE TableReadUnit